perm filename HOSTS2.MID[NET,MRC]4 blob
sn#451563 filedate 1979-06-21 generic text, type T, neo UTF8
;<ADMIN.MRC>HOSTS2.MID.19, 21-Jun-79 00:56:35, Edit by ADMIN.MRC
;-*-MIDAS-*-
TITLE HOSTS2 compiler
IFNDEF ITSSW,ITSSW==IFE <.OSMIDAS-SIXBIT/ITS/>,[-1] .ELSE 0
IFNDEF SAILSW,SAILSW==IFE <.OSMIDAS-SIXBIT/SAIL/>,[-1] .ELSE 0
IFNDEF T20SW,T20SW==IFE <<.OSMIDAS-SIXBIT/TENEX/>&<.OSMIDAS-SIXBIT/TWENEX/>>,[-1] .ELSE 0
;Currently knows about three networks, ARPA, CHAOS, and DIAL. To add additional
;networks, search for all occurrences of these strings and mung the
;code there appropriately. It isn't really practical to make networks
;just be a table, since it has to know how to parse addresses on different
;networks.
;This program .INSRTs the file SYSENG;HOSTS > describing all the network hosts
;and produces a compiled file SYSBIN;HOSTS2 > which network programs read in.
;At SAIL the files are HOSTS.TXT[NET,MRC] and HOSTS2.BIN[NET,MRC].
;For Tops-20 the files are HOSTS.TXT and HOSTS2.BIN.
;The format of the compiled HOSTS2 file is:
HSTSID==:0 ; wd 0 SIXBIT /HOSTS2/
HSTFN1==:1 ; wd 1 SIXBIT /HOSTS/ usually
HSTVRS==:2 ; wd 2 FN2 of HOSTS file which this was compiled from.
HSTDIR==:3 ; wd 3 SIXBIT /SYSENG/ usually, directory name of source file
HSTMCH==:4 ; wd 4 SIXBIT /AI/ (e.g.), device name of source file
HSTWHO==:5 ; wd 5 UNAME of person who compiled this
HSTDAT==:6 ; wd 6 Date of compilation as sixbit YYMMDD
HSTTIM==:7 ; wd 7 Time of compilation as sixbit HHMMSS
NAMPTR==:10 ; wd 10 Address in file of NAME table.
SITPTR==:11 ; wd 11 Address in file of SITE table.
NETPTR==:12 ; wd 12 Address in file of NETWORK table.
;....expandable....
;NETWORK table
; wd 0 Number of entries in table.
; wd 1 Number of words per entry. (2)
;This table contains one entry for each network known about, sorted
;by network number. A network number is bits 4.8-4.1 of a network
;address; these numbers are assigned by Jon Postel. See symbols below.
;The reason for keeping track of different networks is that the user
;program must make different system calls to use each network.
;Each entry contains:
NETNUM==:0 ; wd 0 network number
NTLNAM==:1 ; wd 1 LH - address in file of name of network
NTRTAB==:1 ; wd 1 RH - address in file of network's address table
NETLEN==:2
;ADDRESS table(s)
; wd 0 Number of entries in table.
; wd 1 Number of words per entry. (2)
;There is one of these tables for each network. It contains entries
;for each site attached to that network, sorted by network address.
;These tables are used to convert a numeric address into a host name.
;Also, the list of network addresses for a site is stored
;within these tables.
;Each entry contains:
ADDADR==:0 ; wd 0 Network address of this entry (including network number).
ADLSIT==:1 ; wd 1 LH - address in file of SITE table entry
ADRCDR==:1 ; wd 1 RH - address in file of next ADDRESS entry for this site
; 0 = end of list
ADDLEN==:2
;SITE table
; wd 0 Number of entries in table.
; wd 1 Number of words per entry. (3)
;This table contains entries for each network site,
;not sorted by anything in particular. A site can have more
;than one network address, usually on different networks.
;This is the main, central table.
;Each entry looks like:
STLNAM==:0 ; wd 0 LH - address in file of official host name
STRADR==:0 ; wd 0 RH - address in file of first ADDRESS table entry for this
; site. Successive entries are threaded together
; through ADRCDR.
STLSYS==:1 ; wd 1 LH - address in file of system name (ITS, TIP, TENEX, etc.)
; May be 0 => not known.
STRMCH==:1 ; wd 1 RH - address in file of machine name (PDP10, etc.)
; May be 0 => not known.
STLFLG==:2 ; wd 2 LH - flags:
STFSRV==:400000 ; 4.9 1 => server site (according to NIC)
; wd 2 RH - not used
SITLEN==:3
;NAMES table:
; wd 0 Number of entries
; wd 1 Number of words per entry. (1)
;This table is used to convert host names into network addresses.
; Followed by entries, sorted by the host name treated as a vector of
; signed integers, looking like:
NMLSIT==:0 ; lh address in file of SITE table entry for this host.
NMRNAM==:0 ; rh address in file of host name
;This name is official if NMRNAM = STLNAM of NMLSIT.
NAMLEN==:1
; All names are ASCIZ strings, all letters upper case.
; The strings are stored before, after and between the tables.
; All strings are word-aligned, and fully zero-filled in the last word.
;Network addresses are defined as follows, for purposes of this table:
; 4.9 0
; 4.8-4.1 network number
; Chaos net (number 7):
; 3.9-2.8 0
; 2.7-1.1 address (2.7-1.9 subnet, 1.8-1.1 host)
; Arpa net (number 12): (note, old-format Arpanet addresses
; 3.9-3.8 0 never appear in the host table.)
; 3.7-2.1 Imp
; 1.9 0
; 1.8-1.1 Host
; Dialnet (number 26):
; 3.9-3.1 0
; 2.9-1.1 address in file of ASCIZ string of phone number
NW%CHS==:7 ;Chaos net
NW%ARP==:12 ;Arpa net
NW%DLN==:26 ;Dialnet
NW$BYT==:331000 ;Byte pointer to network number
;Other network address formats accepted elsewhere:
;A network number of 0 defaults the network according to context. "Old
;format" Arpa net addresses, of the form 1.8-1.7 Host, 1.6-1.1 Imp
;The host-table compiler assumes Arpa net if the network number is
;zero, and converts old format Arpa net addresses to new format. The
;NETWRK routines for accessing this table assume a network (for number
;zero) which depends on a program switch, and convert old format Arpa
;net addresses to new format. There will also be a program switch for
;which networks are allowed to be returned from a host name lookup.
;The ITS Arpanet software accepts addresses with or without the network
;number; if the network number is non-zero it must be 12(octal). The
;network number is NOT returned by the system. ITS accepts either old
;or new format addresses, and returns the old format whenever possible.
;The ITS Chaos net software always inputs and outputs addresses in
;16-bit bytes, so the network number issue does not arise.
;Dialnet addresses are always ASCIZ strings.
;The English host table is in the format of one line entries looking
;like: (This is upwards compatible from the present format)
; HOST <name>,<host #s>,<status>,<system>,<machine>,[<nicknames>]
; sorted alphabetically by host name. All fields should be in
; upper case. The fields are:
; <name> official name of this site according to the NIC.
; <host #s> Either a single network address, or a list of network
; addresses enclosed in square brackets and separated
; by commas. A network address consists of an OCTAL
; number, optionally preceeded by a network name and
; a space. Arpa net numbers will accept HOST slash
; IMP in DECIMAL for BBN compatibility. This is
; preferred, for easy data-base interchange. Network
; names currently allowed are CHAOS, ARPA, and DIAL. If no
; network name is specified, then the Arpa net is assumed.
; New style host numbers are represented with the
; 1.1 through 1.8 bits being the host number, and
; the 2.1 through 2.7 bits being the IMP number. For
; example, in the new format MIT-AI (host 2 on IMP 6)
; is represented as 6002.
; <status> whether USER or SERVER. This is usually the
; status "according to the NIC".
; <system> operating system name (eg TENEX, ITS, MULTICS,
; etc). Many elves actually have other systems
; behind them; if possible, the system behind
; the ELF is used rather than the ELF. Also,
; TOPS-10 is used rather than TOPS10. HOSTS2
; (the compiler) will take care of the necessary
; system name mappings.
; <machine> actual machine type (eg PDP10, 370, PDP11, etc).
; By convention, KA-10, KI-10, KL-10, KL-20 and
; MAXC are all considered to be PDP-10s. No -
; should be after "PDP"; this is so it fits in
; one 36-bit word.
; <nicknames> nicknames for this host (whether NIC nicknames
; or local ones). The list is in square brackets
; and each name is delimited by a comma.
;We assemble the network table into a string of entries, of this form:
NWKNUM==:0 ; wd 0 -> network number
NWKNAM==:1 ; wd 1 -> asciz network name
NWKLEN==:2 ;2 words per network entry
;We assemble the host table into a string of entries, of this form:
HSTNAM==:0 ; wd 0 -> asciz host name
HSTNUM==:1 ; wd 1 host number list consed up. 0 terminates list,
; RH is next, LH -> full-word containing number
HSTSRV==:2 ; wd 2 nonzero iff server host
HSTSYS==:3 ; wd 3 -> asciz system name ("TIP" is a system name).
; (may be 0).
HSTMCH==:4 ; wd 4 -> asciz machine name (may be 0).
HSTNIC==:5 ; wd 5 -> nickname list, LISP-style. LH of each word, starting
; with this one itself, -> ASCIZ, RH is next. All zero
; word rather than zero RH terminates list
HSTLEN==:6 ;6 words per host entry.
;AC Defs
F==0
A=1
B=2
C=3
D=4
E=5
G=6
H=7
I=10
J=11
K=12
M=13
N=14 ; used as network table ptr in GHOST
R=15
S=16
P=17
TYOC==17 ;in case error messages
CALL=PUSHJ P,
RET=POPJ P,
SAVE=PUSH P,
REST=POP P,
IFN ITSSW,[
LOC 100 ;absolute assembly
;To make a new version of the HOSTS2 table, :XFILE AI:SYSENG;HOSTS XFILE
;which will run this program with latest host table and
;dump out a new version of the HOSTS2 file.
;1st arg name of system call,
;2nd like a literal has args to call.
DEFINE SYSCAL A,B
.CALL [SETZ ? SIXBIT/A/ ? B ((SETZ))]
TERMIN
INCH==1 ;Input channel
];IFN ITSSW
IFN T20SW,[
.DECSAV
LOC 140 ; absolute assembly
DEFINE .VALUE
JRST 4,.-1
TERMIN
];IFN T20SW
IFN SAILSW,[
;To make a new version of the HOSTS2 table, BATCH/NOW @HOSTS
;which will run this program with latest host table and
;dump out a new version of the HOSTS2 file.
DEFINE .VALUE
JRST 4,.-1
TERMIN
IF1,[ ;name conflict with WAITS
OUTUUO=OUT
EXPUNGE OUT
];IF1
];IFN SAILSW
LPDL==40
PDL: BLOCK LPDL+10
PATCH: PAT: BLOCK 40
;Write out the compiled file.
DUMP: MOVE P,[-LPDL,,PDL-1]
IFN ITSSW,[
.OPEN TYOC,[.UAO,,'TTY]
.LOSE %LSFIL
.CORE <CORTOP+1777>/2000
.LOSE
.SUSET [.RUNAME,,UNAME]
.RDATE A, ;Init the auditing info at the front
MOVEM A,$DATE ;Name conflict with WAITS
.RTIME A,
MOVEM A,$TIME
];IFN ITSSW
IFN T20SW,[
SETZM OUTEND
MOVE A,[OUTEND,,OUTEND+1]
BLT A,CORTOP-1
MOVE A,['TOPS20]
MOVEM A,UNAME
SETO B,
SETZ D,
ODCNV
HLRZ E,B
SUBI E,1900.
IDIVI E,10.
ADDI E,'0
ADDI G,'0
DPB E,[360600,,$DATE]
DPB G,[300600,,$DATE]
MOVEI E,1(B)
IDIVI E,10.
ADDI E,'0
ADDI G,'0
DPB E,[220600,,$DATE]
DPB G,[140600,,$DATE]
HLRZ E,C
ADDI E,1
IDIVI E,10.
ADDI E,'0
ADDI G,'0
DPB E,[060600,,$DATE]
DPB G,[000600,,$DATE]
MOVEI B,(D)
IDIVI B,60.*60.
IDIVI C,60.
PUSH P,C
IDIVI B,10.
MOVEI A,'0(B)
LSH A,6
ADDI A,'0(C)
POP P,B
IDIVI B,10.
LSH A,6
ADDI A,'0(B)
LSH A,6
ADDI A,'0(C)
IDIVI D,10.
LSH A,6
ADDI A,'0(D)
LSH A,6
ADDI A,'0(E)
MOVEM A,$TIME
];IFN T20SW
IFN SAILSW,[
MOVEI A,CORTOP
MOVEM A,JOBFF
CORE A,
.VALUE
SETZM OUTEND
MOVE A,[OUTEND,,OUTEND+1]
BLT A,CORTOP-1
GETPPN A,
CAI ;Fastest no-op in the West!
HRLZM A,UNAME
DATE B,
IDIVI B,12.*31.
ADDI B,64.
IDIVI C,31.
ADDI C,1
ADDI D,1
PUSH P,C
IDIVI B,10.
MOVEI A,'0(B)
LSH A,6
ADDI A,'0(C)
POP P,B
IDIVI B,10.
LSH A,6
ADDI A,'0(B)
LSH A,6
ADDI A,'0(C)
IDIVI D,10.
LSH A,6
ADDI A,'0(D)
LSH A,6
ADDI A,'0(E)
MOVEM A,$DATE
MSTIME B,
IDIVI B,1000.
IDIVI B,60.*60.
IDIVI C,60.
PUSH P,C
IDIVI B,10.
MOVEI A,'0(B)
LSH A,6
ADDI A,'0(C)
POP P,B
IDIVI B,10.
LSH A,6
ADDI A,'0(B)
LSH A,6
ADDI A,'0(C)
IDIVI D,10.
LSH A,6
ADDI A,'0(D)
LSH A,6
ADDI A,'0(E)
MOVEM A,$TIME
];IFN SAILSW
CALL RHOSTF ;Read in the HOSTS file
; JRST UPPER ;Drops through to next page
;Now convert all system, machine and host names to upper case.
;This is so that user programs can search and compare more easily.
;Also, it makes sure that CANON really maps all instances of a system
;or machine name into the same name.
UPPER: MOVEI A,HSTTAB
UPPER1: MOVE B,HSTSYS(A)
CALL UPPERS
MOVE B,HSTMCH(A)
CALL UPPERS
MOVE B,HSTNAM(A)
CALL UPPERS
MOVE C,HSTNIC(A) ;Get nickname list
JUMPE C,UPPER3 ;empty
UPPER2: HLRZ B,C ;CAR
CALL UPPERS ;and convert each nickname in it.
SKIPE C,(C) ;CDR
JRST UPPER2
UPPER3: ADDI A,HSTLEN ;Advance to next host.
CAME A,HSTTBE
JRST UPPER1
MOVEI A,NWKTAB ;Now do it to the network names
UPPERN: MOVE B,NWKNAM(A)
CALL UPPERS
ADDI A,NWKLEN
CAME A,NWKTBE
JRST UPPERN
JRST CANON
;Convert the the ASCIZ string that B points to to upper case,
;modifying it in place. Clobbers B and E.
UPPERS: HRLI B,440700
UPPER4: ILDB E,B
JUMPE E,CPOPJ
CAIL E,"a
CAILE E,"z
JRST UPPER4
SUBI E,"a-"A
DPB E,B
JRST UPPER4
;Now store the System name strings into the file, storing each
;distinct name only once. We replace each System name pointer
;with a pointer (in our address space) to the string stored
;into the file (the "interned" string) so we don't have to search
;the file when we write the SITES table.
;Also, G counts how many words of space will be needed for all
;the host names and nicknames.
CANON: MOVEI A,SYSNMS ;A is storing pointer for new system names. (COMMENT IS WRONG)
MOVEI B,HSTTAB ;B points at data of next host to hack.
SETZB G,H
CNTLP: SKIPE C,HSTSYS(B) ;Store the system name if necessary.
CALL CONSNM
SKIPE HSTSYS(B)
MOVEM J,HSTSYS(B) ;replace system name string with interned one.
SKIPE C,HSTMCH(B)
CALL CONSNM ;Do the same thing with the machine name.
SKIPE HSTMCH(B)
MOVEM J,HSTMCH(B)
HRRZ E,HSTNUM(B) ;ptr to host number list
CNTLD: HLRZ C,(E) ;ptr to first host number
MOVE C,(C) ;hst number
LDB D,[NW$BYT,,C] ;Dialnet needs ASCII hackery
;Actually, this routine can be used for any ASCII host "number"
CAIE D,NW%DLN
JRST CNTLND ;Not Dialnet
PUSH P,E ;Save ptr since NAMCPY stomps on it
CALL NAMCPY ;Copy the string into our core area
HLRZ C,@(P) ;ptr to address
HRRM E,(C) ;step on hst number
POP P,E
CNTLND: HRRZ E,(E) ;Not Dialnet, try next
JUMPN E,CNTLD ;Loop back for more addresses
MOVE C,HSTNAM(B)
CALL COUNT ;Count space official name will take,
MOVE D,HSTNIC(B) ;and space the nicknames will take.
AOS H ;H counts number of names and nicknames.
JUMPE D,CNTLP2
CNTLP1: HLRZ C,D ;CAR
CALL COUNT
AOS H ;H counts number of names and nicknames.
SKIPE D,(D) ;CDR
JRST CNTLP1
CNTLP2: ADDI B,HSTLEN
CAMGE B,HSTTBE
JRST CNTLP
MOVEI B,NWKTAB ;Count space for network names
SKIPE C,1(B)
JRST [ CALL COUNT
ADDI B,NWKLEN
JRST .-1]
ADD G,OUTPT ;End of name strings, start of tables
MOVEM G,ENDHSN'
IRPS NET,,[ARPA CHAOS DIAL]
MOVE A,G
SUBI A,OUT
MOVEM A,AD!NET
SETZM (G) ;Let BAT AOS the number of entries
MOVEI A,ADDLEN
MOVEM A,1(G)
ADDI G,2 ;Header words
MOVE M,N!NET
IMULI M,ADDLEN ;Size of this table
ADD G,M ;Address of next table
TERMIN
MOVEM G,NETP ;NETWORK table starts here
MOVE M,NNETS
MOVEM M,(G) ;Number of entries in NETWORK table
MOVEI A,NWKLEN
MOVEM A,1(G) ;Number of works per entry
IMUL M,A ;Compute total length
ADDI G,2(M) ;And thus the position of ADDRESS table
MOVEM G,SITP ;SITES table starts after ADDRESS tables
MOVE M,NHOSTS
MOVEM M,(G) ;Store number of entries in SITES table.
MOVEI A,SITLEN
MOVEM A,1(G) ;Store number of words per entry.
IMUL M,A ;Compute total length
ADDI M,2(G) ;and thus the position of NAMES table.
MOVEM M,NAMEP
MOVEM M,NAMP
MOVEM H,@NAMEP ;Store size of NAMES table (= # of hosts + nicknames)
AOS NAMEP ;in its 1st word, and advance storing pointer.
MOVEI H,1 ;Number of words per entry
MOVEM H,@NAMEP ;in 2nd word
AOS NAMEP ;Storing pointer for entries
SUBI G,OUT
MOVEM G,SITPR
SUBI M,OUT
MOVEM M,NAMPR
MOVE A,NETP
SUBI A,OUT
MOVEM A,NETPR
JRST MACH ;Go figure out machine names if possible.
;C -> an ASCIZ string. Add to G the number of words it occupies.
;Clobbers E.
COUNT: MOVE E,(C)
AOS G
TRNN E,376
RET
AOJA C,COUNT
;C -> an ASCIZ string; intern it in the system names table.
;If the table has no string EQUAL to the arg, make a new one at the end.
;In either case, return in J the address of the interned string.
;A -> the beginning of the system names table, and OUTPT -> the end.
;Clobbers D, E, and K.
CONSNM: MOVE E,A ;E looks at all strings in table, 1 by 1.
CONSLP: MOVE J,E
CAMN E,OUTPT ;Reached start of next string in table
JRST CONSLS ; but maybe it's the end of table.
MOVE K,C
CONSCM: MOVE D,(K)
CAME D,(E) ;Compare table string agains our arg word
JRST CONSNX ;by word. No match => skip to next string
TRNN D,376 ;in table. Match until end of ASCIZ =>
RET ;we found the arg in the table.
AOS E ;else compare next words of the two strings.
AOJA K,CONSCM
CONSNX: MOVE K,(E) ;Advance to start of next ASCIZ string in table
TRNN K,376
AOJA E,CONSLP ;then compare it against our arg.
AOJA E,CONSNX
CONSLS: MOVE D,(C) ;String not found in table, so copy it
MOVEM D,@OUTPT ;to the end of the table.
AOS OUTPT
TRNE D,376
AOJA C,CONSLS
RET
;Now figure out the type of machine from the system name, if possible,
;in case HOSTS currently has no info on machine type.
MACH: MOVEI A,HSTTAB
MACHL: MOVE B,HSTSYS(A)
CAIE B,TEN50
CAIN B,TOPS10
MOVEI B,BOTS10 ;Canonicalize system name.
CAIN B,TOPS20
MOVEI B,TWENEX
MOVEM B,HSTSYS(A)
SKIPE C,HSTMCH(A) ;If machine type not already known,
JRST MACHNX ;try to determine it from system name.
CAIE B,ITS
CAIN B,TENEX
MOVEI C,PDP10
CAIE B,TOPS10
CAIN B,TOPS20
MOVEI C,PDP10
CAIE B,SAIL
CAIN B,TEN50
MOVEI C,PDP10
CAIE B,BOTS10
CAIN B,TWENEX
MOVEI C,PDP10
CAIN B,TIP
MOVEI C,TIP
CAIN B,MULTIC
MOVEI C,MULTIC
CAIE B,HYDRA
CAIN B,RSX11
MOVEI C,PDP11
CAIE B,ELF
CAIN B,UNIX
MOVEI C,PDP11
MOVEM C,HSTMCH(A)
MACHNX: ADDI A,HSTLEN
CAME A,HSTTBE
JRST MACHL
; JRST BNT ;Build sorted NETWORK table
; Good morning Mr. Phelps. Your mission, should you decide to accept it, is to
; think about network names. As usual, if you or any of your colleagues are
; captured during this mission, the secretary will disavow any knowledge of your
; actions. This comment will self-destruct in 5 seconds. Good luck Jim.
BNT: MOVEI N,NWKTAB ;Source
MOVE C,NNETS ;Number of times to do
MOVE A,NETP ;Destination
ADDI A,2 ;Skip header
BNT1: MOVE D,NWKNUM(N) ;Network number
MOVEM D,NETNUM(A)
SAVE C
HRRZ C,NWKNAM(N) ;Now the name
CALL NAMCPY
REST C
HRLZM E,NTLNAM(A)
; Set up NT pointer for the ADDRESS tables to fill in
MOVE D,NETNUM(A)
MOVEI M,NTRTAB(A)
IRPS NET,,[ARPA CHAOS DIAL]NUM,,[NW%ARP NW%CHS NW%DLN]
CAIE D,NUM
JRST .+4
MOVEM M,NT!NET
MOVE M,AD!NET ;Also set up pointer to ADDRESS block
HRRM M,NTRTAB(A)
TERMIN
ADDI A,NETLEN ;Next slot in line
ADDI N,NWKLEN ;Done with this network, try next
SOJG C,BNT1
; JRST BAT ;Build sorted ADDRESS tables
;Now build the sorted ADDRESS tables
;First stage is just to fill in all the numbers, using insertion sort.
;Second stage is to fill in the address lists and SITE pointers.
BAT: MOVEI A,HSTTAB ;For each host
BAT0: HRRZ B,HSTNUM(A) ;For each address of that host
JUMPN B,BAT1
MOVE A,HSTNAM(A) ;If no addresses, barf
PUSHJ P,ASZOUT
MOVEI A,[ASCIZ/ has no addresses/]
PUSHJ P,ASZOUT
.VALUE
BAT1: HLRZ E,(B) ;CAR
MOVE E,(E) ;Is address
LDB C,[NW$BYT,,E] ;Get network number, convert to ADDRESS table address
SETO D,
IRPS NAME,,[ARPA CHAOS DIAL]NUM,,[NW%ARP NW%CHS NW%DLN]
CAIN C,NUM
MOVE D,NT!NAME
TERMIN
SKIPGE D
.VALUE ;Garbage network number?
MOVE D,(D)
AOS C,OUT(D) ;Get 1+ number of entries in table
SUBI C,1
IMULI C,ADDLEN ;Index into table of last+1 entry
ADDI C,OUT+2(D) ;Address
MOVE M,C ;Save upper bound
BAT2: SUBI C,ADDLEN ;Next guy to compare against
CAIGE C,OUT+2(D) ;Anybody there?
JRST BAT3 ;No, put this one in at bottom of table
CAMN E,(C)
JRST [ MOVE A,HSTNAM(A)
PUSHJ P,ASZOUT
MOVEI A,[ASCIZ/ duplicate address /]
PUSHJ P,ASZOUT
MOVE A,E
PUSHJ P,OCTOUT
MOVEI A,[ASCIZ/ octal/]
PUSHJ P,ASZOUT
.VALUE ]
CAMG E,(C) ;Does new guy go after this one?
JRST BAT2 ;No, keep looking
;Address in C is last guy before new guy
;Blt (C)+ADDLEN ... (M)-ADDLEN up by ADDLEN
BAT3: ADDI C,ADDLEN ;First guy to move up, also where new frob goes
BAT4: MOVE G,ADDADR-ADDLEN(M)
MOVEM G,ADDADR(M)
SUBI M,ADDLEN
CAML M,C
JRST BAT4
MOVEM E,ADDADR(C) ;Store new guy
HRRZ B,(B) ;CDR
JUMPN B,BAT1
ADDI A,HSTLEN ;Next host
CAMGE A,HSTTBE
JRST BAT0
IRPS NAME,,[ARPA CHAOS DIAL] ;Verify correct length of tables
HRRZ A,NT!NAME
MOVE A,(A)
MOVE A,OUT(A) ;Number of entries ended up in table
CAME A,N!NAME
.VALUE
TERMIN
; JRST MT ;Now build SITE table and fill in rest of ADDRESS tables
;Now build the contents of the SITE table, which does not need to be sorted.
MT: MOVEI B,HSTTAB ;B points at data of next host to hack.
MOVE A,SITP
ADDI A,2 ;A is pointer for storing SITES table entries.
MTLP: SKIPE E,HSTSYS(B)
SUBI E,OUT ;Store ptr to system name (in file addr space).
HRLZM E,STLSYS(A)
SKIPE E,HSTMCH(B)
SUBI E,OUT
HRRM E,STRMCH(A) ;and the machine name.
MOVEI E,0 ;STLFLG and unused RH
SKIPE HSTSRV(B) ;If a server host, set the flag for that.
TLO E,STFSRV
MOVEM E,STLFLG(A)
MOVE C,HSTNAM(B)
CALL NAMCPY ;Copy the host name to where OUTPT points,
HRLZM E,STLNAM(A) ;and store a pointer to the copy.
;; For each address of this site, find and complete ADDRESS table entry
;; Also, make STRADR point to list of them
HRRZ C,HSTNUM(B) ;List of addresses
MT1: HLRZ D,(C) ;CAR
MOVE D,(D) ;Network address
LDB E,[NW$BYT,,D] ;Get network number, convert to ADDRESS table address
SETO G,
IRPS NAME,,[ARPA CHAOS DIAL]NUM,,[NW%ARP NW%CHS NW%DLN]
CAIN E,NUM
HRRZ G,NT!NAME
TERMIN
SKIPGE G
.VALUE ;Garbage network number?
MOVE G,(G)
SKIPG H,OUT(G) ;Number of entries
.VALUE ;Hmm, not prepared to deal with empty tables
ADDI G,OUT+2 ;Start of ADDRESS table entries
MT2: CAMN D,ADDADR(G) ;Linear search for specified number
JRST MT3
ADDI G,ADDLEN
SOJG H,MT2
.VALUE ;Foo
MT3: HRRZ H,STRADR(A) ;CONS onto STRADR
HRRM H,ADRCDR(G) ;Threaded through ADRCDR
IFN ITSSW\T20SW,[
MOVEI H,-OUT(G) ;Make each guy point to other
HRRM H,STRADR(A)
MOVEI H,-OUT(A)
HRLM H,ADLSIT(G)
];IFN ITSSW\T20SW
IFN SAILSW,[
MOVEI H,(G)
SUBI H,OUT
HRRM H,STRADR(A)
MOVEI H,(A)
SUBI H,OUT
HRLM H,ADLSIT(G)
];IFN SAILSW
HRRZ C,(C) ;CDR
JUMPN C,MT1
MOVEM A,HSTNAM(B) ;Clobber host name with site ptr for later use
ADDI A,SITLEN ;Advance A to store next entry next time.
ADDI B,HSTLEN
CAMGE B,HSTTBE
JRST MTLP
CAME A,NAMP ;Check that SITES table occupies expected
.VALUE ;amount of space.
SUB A,SITP
SUBI A,2
MOVE B,@SITP ;Check that right number of SITES
IMULI B,SITLEN ;entries were made.
CAME A,B
.VALUE
JRST MNAM
;Copy ASCIZ string <- C to where OUTPT points, advancing OUTPT.
;Return in E the address of the copy, in file address space.
NAMCPY: MOVE E,OUTPT
SUBI E,OUT
SAVE E
MTE1: MOVE E,(C)
MOVEM E,@OUTPT
AOS OUTPT
TRNE E,376
AOJA C,MTE1
REST E
RET
;Now that the SITES table is finished, we can make the NAMES
;table, which has pointers into the SITES table.
MNAM: MOVEI B,HSTTAB ;Driven by HSTTAB
MNAML: MOVE A,HSTNAM(B) ;HSTNAM now points to SITES table
IFN ITSSW\T20SW,HRLZI E,-OUT(A) ;Make the official name's entry. Get SITES entry addr in lh.
IFN SAILSW,[
MOVEI D,(A) ;This allows reloation so can debug with RAID
SUBI D,OUT
HRLZI E,(D)
];IFN SAILSW
HLR E,STLNAM(A) ;Put ptr to host name in rh (copy from SITES entry).
MOVEM E,@NAMEP ;NMLSIT,,NMRNAM
AOS NAMEP
MOVE D,HSTNIC(B) ;D points to list of nickname pointers.
JUMPE D,MNAMX
MNAMN: HLRZ C,D ;C gets the next nickname. (CAR)
CALL NAMCPY ;Copy the nickname into file, E gets addr of copy.
IFN ITSSW\T20SW,[
HRLI E,-OUT(A) ; Get SITES entry addr in lh.
];IFN ITSSW\T20SW
MOVEM E,@NAMEP
IFN SAILSW,[
MOVEI E,(A) ;This allows relocation so can debug with RAID
SUBI E,OUT
HRLM E,@NAMEP
];IFN SAILSW
AOS NAMEP
SKIPE D,(D) ;CDR
JRST MNAMN
MNAMX: ADDI B,HSTLEN ;Finished making NAMES entry for this host. Hack the next.
CAMGE B,HSTTBE
JRST MNAML
MOVE B,NAMEP ;Check that expected number of NAMES
SUB B,NAMP ;entries were made.
SUBI B,2
CAME B,@NAMP
.VALUE
MOVE B,OUTPT ;Check that host names exactly filled
CAME B,ENDHSN ;the space allotted.
.VALUE
JRST SNAM ;Now go sort this table.
;Sort the NAMES table.
SNAM: SETZ B, ;No exchanges yet this pass.
MOVE A,NAMP ;A is pointer for scanning through.
ADDI A,2
MOVE G,NAMEP ;G -> next to the last NAMES entry.
SUBI G,2
SNAML: HRRZ C,NMRNAM(A) ;Get this entry's name and next entry's.
HRRZ D,NMRNAM+NAMLEN(A)
ADDI C,OUT ;Convert file's address space to ours.
ADDI D,OUT
CALL COMPAR ;Skip if these two entries mis-ordered.
JRST SNAMWN
SETO B,
MOVE E,(A)
EXCH E,NAMLEN(A)
MOVEM E,(A)
SNAMWN: CAME A,G ;Each pass scan whole table.
AOJA A,SNAML ;If we exchanged, we need another pass.
JUMPN B,SNAM
; JRST WRITE
;Now write out the compiled hosts file.
IFN ITSSW,[
WRITE: SYSCAL OPEN,[[.UIO,,] ? DMPDEV ? DMPFN1 ? DMPFN2 ? DMPSNM]
.LOSE %LSFIL
MOVE A,[444400,,OUT] ;get BP to data in core,
MOVE B,NAMEP
SUBI B,OUT ;and size of file.
SYSCAL SIOT,[1000,, ? A ? B]
.LOSE %LSSYS
.CLOSE ;write and close, and we're done.
.LOGOUT 1,
;These are the filenames to write.
DMPDEV: SIXBIT /DSK/
DMPFN1: SIXBIT /HOSTS2/
DMPFN2: SIXBIT />/
DMPSNM: SIXBIT /SYSBIN/
];IFN ITSSW
IFN T20SW,[
WRITE: MOVSI A,(GJ%SHT)
HRROI B,[ASCIZ/HOSTS2.BIN/]
GTJFN
.VALUE
MOVE B,[<440000,,0>\OF%WR]
OPENF
.VALUE
MOVE B,[444400,,OUT]
MOVE C,NAMEP
SUBI C,OUT ;size of file.
SOUT
SETO A,
CLOSF
.VALUE
HALTF
JRST .-1
];IFN T20SW
IFN SAILSW,[
WRITE: OPEN [17 ? 'DSK,, ? 0]
.VALUE
ENTER DMPFN1
.VALUE
MOVE B,NAMEP
SUBI B,OUT+1 ;and size of file.
HRLO A,B
EQVI A,OUT-1
SETZ B,
OUTUUO A
CAIA
.VALUE
CLOSE ;write and close
EXIT
;These are the filenames to write.
DMPFN1: SIXBIT /HOSTS2/
DMPFN2: SIXBIT /BIN/
0
DMPSNM: SIXBIT /NETMRC/
];IFN SAILSW
;Compare two ASCIZ strings as vectors of signed integers.
;C -> first string, D -> second. Skip if first is greater.
;If the strings are EQUAL, we barf.
COMPAR: MOVEM C,COMPR1'
MOVEM D,COMPR2'
CMPRLP: MOVE E,(C)
CAMGE E,(D)
RET
CAMLE E,(D)
JRST POPJ1
TRNN E,376 ;Two host names are EQUAL???
JRST CMPRBF
AOS C
AOJA D,CMPRLP
CMPRBF: MOVEI A,[ASCIZ/Two equal host names? /]
PUSHJ P,ASZOUT
MOVE A,COMPR1
PUSHJ P,ASZOUT
MOVEI A,[ASCIZ/ and /]
PUSHJ P,ASZOUT
MOVE A,COMPR2
PUSHJ P,ASZOUT
MOVEI A,[ASCIZ/
/]
PUSHJ P,ASZOUT
.VALUE
POPJ1: AOS (P)
CPOPJ: RET
;Midas doesn't really make it for parsing this hosts table.
;Here's the new frob.
;Get character in A
RCH:
IFN ITSSW,[
SKIPGE A,UNRCHF'
.IOT INCH,A
JUMPE A,.-1 ;SAIL might put nulls in the file?
HRRZS A ;Flush -1 in LH of EOF ↑C
];IFN ITSSW
IFN T20SW,[
SKIPL A,UNRCHF'
JRST RCH1
PUSH P,B
MOVE A,INPJFN
RCH2: BIN
ERJMP [MOVEI A,↑C ;when eof happens, put in ITSish EOF
JRST RCH3]
JUMPE B,RCH2
MOVEI A,(B)
RCH3: POP P,B
RCH1:
];IFN T20SW
IFN SAILSW,[
SKIPL A,UNRCHF'
JRST RCH1
RCH2: SOSG IBUFH+2
IN
CAIA
SKIPA A,[↑C]
ILDB A,IBUFH+1
JUMPE A,RCH2
RCH1:
];IFN SAILSW
CAIN A,↑J ;Count lines
SKIPL UNRCHF
CAIA
AOS LINENO'
SETOM UNRCHF
RET
;Returns in A positive character (SCO), ↑C at eof, or negative BP to ASCIZ string
;Bash B
RTOKEN: CALL RCH ;First, skip white space and comments
CAIN A,↑C
RET ;EOF
CAIN A,";
JRST RTOKCM
CAIN A,↑J ;LF is an SCO
RET
CAIG A,40
JRST RTOKEN ;White space
CAIN A,", ;Comma is an SCO
RET
CAIE A,"[ ;Brackets are SCO
CAIN A,"]
RET
;; OK, this is going to be a long symbol
MOVE B,TOKBP ;Start of this symbol
RTOK1: IDPB A,TOKBP
CALL RCH
CAILE A,40 ;Check for termination
CAIN A,";
JRST RTOK2
CAIN A,",
JRST RTOK2
CAIE A,"[
CAIN A,"]
JRST RTOK2
JRST RTOK1
RTOK2: MOVEM A,UNRCHF
MOVEI A,0
IDPB A,TOKBP
MOVE A,B ;Return value is negative BP to ASCIZ
AOS B,TOKBP ;Advance BP to next word
HRLI B,440700
MOVEM B,TOKBP
RET
RTOKCM: CALL RCH ;Skip comment
CAIE A,↑J ;Which turns into CRLF
CAIN A,↑C ;EOF Shouldn't happen
RET
JRST RTOKCM
;Require a comma here, or a CRLF. Skip if comma
RCOMLF: CALL RTOKEN
CAIN A,↑J
RET
CAIN A,",
JRST POPJ1
MOVEI A,[ASCIZ/Missing comma or CRLF/]
JRST BARF
;Require a comma here
RCOMMA: CALL RTOKEN
CAIN A,",
RET
MOVEI A,[ASCIZ/Missing comma/]
JRST BARF
BARF: PUSHJ P,ASZOUT
MOVEI A,[ASCIZ/
Error near line #/]
PUSHJ P,ASZOUT
MOVE A,LINENO
PUSHJ P,DECOUT
.VALUE
ASZOUT:
IFN T20SW,[
HRLI A,-1
PSOUT
RET
];IFN T20SW
IFN SAILSW,[
OUTSTR (A)
RET
];SAILSW
IFN ITSSW,[
HRLI A,440700
ASZOU1: ILDB B,A
JUMPE B,CPOPJ
.IOT TYOC,B
JRST ASZOU1
];IFN ITSSW
DECOUT: IDIVI A,10.
HRLM B,(P)
SKIPE A
PUSHJ P,DECOUT
HLRZ A,(P)
ADDI A,"0
IFN ITSSW, .IOT TYOC,A
IFN SAILSW, OUTCHR A
IFN T20SW,PBOUT
RET
OCTOUT: IDIVI A,8
HRLM B,(P)
SKIPE A
PUSHJ P,OCTOUT
HLRZ A,(P)
ADDI A,"0
IFN ITSSW, .IOT TYOC,A
IFN T20SW,PBOUT
IFN SAILSW, OUTCHR A
RET
;; This guy is called to read HOST lines. Store indirect through D.
GHOST: CALL RTOKEN ;Should be HOST
JUMPL A,GHOST1 ;If SCO, hopefully EOF or blank line
CAIN A,↑J
JRST GHOST
CAIN A,↑C
RET
GHOSTE: MOVEI A,[ASCIZ/Randomness when expecting HOST/]
JRST BARF
GNET: CALL RTOKEN ;Next should be network name
JUMPGE A,[ MOVEI A,[ASCIZ/Random character when expecting net name/]
JRST BARF]
MOVEM A,NWKNAM(N)
CALL RCOMMA
CALL RTOKEN
SETZ C, ;Net number not got yet
GNET1: ILDB B,A
CAIL B,"0
CAILE B,"9
JRST GNET2
IMULI C,10.
ADDI C,-"0(B)
JRST GNET1
GNET2: JUMPN B,[ MOVEI A,[ASCIZ/Random character when expecting net number/]
JRST BARF]
MOVEM C,NWKNUM(N)
CALL RTOKEN
CAIE A,↑J ;Should be end of line
JRST [ MOVEI A,[ASCIZ/Garbage where end of line expected/]
JRST BARF]
ADDI N,NWKLEN
AOS NNETS
JRST GHOST
GHOST1: MOVE B,(A)
CAMN B,[ASCIZ/NET/]
JRST GNET
CAME B,[ASCIZ/HOST/]
JRST GHOSTE
CALL RTOKEN ;Next should be host name
JUMPGE A,[ MOVEI A,[ASCIZ/Random character when expecting host name/]
JRST BARF ]
MOVEM A,HSTNAM(D)
CALL RCOMMA ;Next should be comma
SETZM HSTNUM(D) ;Host number list empty (initially)
CALL RTOKEN ;Should be either a host# or a bracketed list of such
CAIE A,"[ ;]
JRST [ CALL GHOSTN
JRST GHOST3 ]
GHOST2: CALL RTOKEN
CALL GHOSTN ;
CALL RTOKEN
CAIN A,",
JRST GHOST2 ;[
CAIE A,"]
JRST [ MOVEI A,[ASCIZ/Missing close bracket/]
JRST BARF ]
GHOST3: CALL RCOMMA ;Next a comma
CALL RTOKEN ;Status
MOVE B,(A)
SETZM HSTSRV(D)
CAMN B,[ASCII/SERVE/]
SETOM HSTSRV(D)
CALL RCOMLF
JRST GHOST6 ;CRLF
CALL RTOKEN ;Optional system name
JUMPGE A,[ SETZM HSTSYS(D)
MOVEM A,UNRCHF
JRST .+2 ]
MOVEM A,HSTSYS(D)
CALL RCOMLF
JRST GHOST6 ;CRLF
CALL RTOKEN ;Optional machine name
JUMPGE A,[ SETZM HSTMCH(D)
JRST .+3 ]
MOVEM A,HSTMCH(D)
CALL RTOKEN
;Here A is comma before nicknames, or CRLF
SETZM HSTNIC(D)
CAIE A,",
JRST GHOST6
CALL RTOKEN ;Single nickname or bracket that begins list
CAIE A,"[ ;]
JRST [ CALL GNICKN
JRST GHOST5 ]
GHOST4: CALL RTOKEN
CALL GNICKN
CALL RTOKEN
CAIN A,",
JRST GHOST4 ;[
CAIE A,"]
JRST [ MOVEI A,[ASCIZ/Missing close bracket/]
JRST BARF ]
GHOST5: CALL RTOKEN
GHOST6: CAIE A,↑J ;Should be end of line
JRST [ MOVEI A,[ASCIZ/Garbage where end of line expected/]
JRST BARF ]
ADDI D,HSTLEN
AOS NHOSTS
JRST GHOST
;;; This parses up a host number and conses it onto list in HSTNUM(D)
;;; First token is in A
GHOSTN: MOVEI B,NW%ARP ;Default to Arpanet
MOVEM B,GHSNNW'
GHSTN0: JUMPGE A,GHSTN9 ;SCO?
ILDB B,A ;First char tells whether it's a number
CAIL B,"0
CAILE B,"9
JRST GHSTN5
MOVEM A,GHSNBP' ;Save ptr to this number
MOVEI C,0 ;It's a number, read in as octal in C
GHSTN1: LSH C,3
ADDI C,-"0(B)
ILDB B,A
JUMPE B,GHSTN8 ;Clearly an Arpanet guy, go store from C
CAIE B,"/ ;Slash allowed in numbers for host slash imp frob
JRST GHSTN1
MOVE A,GHSNBP ;Oh dear. Rescan the number in decimal
LDB B,A
MOVEI C,0
GHSTN2: IMULI C,10.
ADDI C,-"0(B)
ILDB B,A
CAIE B,"/
JRST GHSTN2
PUSH P,C ;Save host number
MOVEI C,0 ;It's a number, read in as decimal in C
ILDB B,A
CAIL B,"0
CAILE B,"9
JRST [MOVEI A,[ASCIZ/Random character in number/]
JRST BARF ]
GHSTN3: IMULI C,10.
ADDI C,-"0(B)
ILDB B,A
JUMPN B,GHSTN3
POP P,B ;B host, C imp.
LSH C,9 ;New format result to C
ADDI C,(B)
MOVEI A,[ASCIZ/Slash notation for non-Arpanet host number/]
MOVE B,GHSNNW
CAIE B,NW%ARP
JRST BARF
;Store number from C
GHSTN8: MOVE B,GHSNNW ;Get network number
CAIN C,NW%ARP ;Canonicalize to new format if Arpanet
CAIL C,1000
JRST GHSTN7
LDB B,[060200,,C] ;B host
ANDI C,77 ;C IMP
LSH C,9
IOR C,B
MOVEI B,NW%ARP
GHSTN7: DPB B,[NW$BYT,,C] ;Put network number into host number
CAIN B,NW%ARP
AOS NARPA ;Count number of Arpa network addresses
CAIN B,NW%CHS
AOS NCHAOS ;Count number of Chaos network addresses
CAIN B,NW%DLN
AOS NDIAL ;Count number of Dialnet network addresses
MOVE B,TOKBP ;2 words to CONS into
MOVEM C,1(B) ;Full word of host number
MOVSI C,1(B) ;car,,cdr
HRR C,HSTNUM(D)
MOVEM C,0(B)
HRRZM B,HSTNUM(D)
ADDI B,2
MOVEM B,TOKBP
RET
GHSTN5: MOVE B,(A) ;Must be a network name
IRPS NAME,,[ARPA CHAOS]NUMBER,,[NW%ARP NW%CHS]
MOVEI C,NUMBER
CAMN B,[ASCII/NAME/]
JRST GHSTN6
TERMIN
CAMN B,[ASCII/DIAL/]
JRST GHSTDL
MOVEI A,[ASCIZ/Unknown network name/]
JRST BARF
GHSTN6: MOVEM C,GHSNNW ;Store network number for later
CALL RTOKEN ;Next token is site number
JRST GHSTN0
GHSTN9: MOVEI A,[ASCIZ/Random character in host number/]
JRST BARF
GHSTDL: CALL RTOKEN
JUMPGE A,GHSTN9 ;SCO?
MOVEI B,NW%DLN ;Dialnet's number
MOVEI C,(A) ;Address of string
JRST GHSTN7
;Get a nickname. Make HSTNIC be pointer to vector of addresses of ASCIZ, end by zero.
;Nick name is already in A, just needs to be CONSed onto list.
GNICKN: MOVSS A ;CAR is in LH
HRR A,TOKBP ;CDR is next free loc
EXCH A,HSTNIC(D) ;Store first CONS, get set to store previous
MOVEM A,@TOKBP ;Store previous
AOS TOKBP ;Bump free ptr
RET
;; Here to read in and parse the hosts file, making HSTTAB and various ASCIZ strings
UPSIZE==6 ;Number of K for upper
HTSIZE==2 ;Number of K for host table
NTSIZE==1 ;Number of K for network table
IFN ITSSW,[
RHOSTF: MOVE A,[-UPSIZE,,HSTTAB/2000] ;6K should be enough core
SYSCAL CORBLK,[MOVEI %CBNDW ? MOVEI %JSELF ? A ? MOVEI %JSNEW ]
.LOSE %LSSYS
SETZM HSTTAB ;Always a good idea
MOVE A,[HSTTAB,,HSTTAB+1]
BLT A,<HSTTAB+UPSIZE*2000>-1
MOVE A,[440700,,HSTTAB+2000*<HTSIZE+NTSIZE>];rest is ASCIZ strings
MOVEM A,TOKBP'
SYSCAL OPEN,[[.UAI,,INCH] ? [SIXBIT/DSK/]
[SIXBIT/HOSTS/] ? [SIXBIT/>/] ? [SIXBIT/SYSENG/]]
.LOSE %LSFIL
MOVEI D,HSTTAB ;Store indirect through D
MOVEI N,HSTTAB+HTSIZE*2000
CALL GHOST
MOVEM D,HSTTBE'
MOVEM N,NWKTBE'
CAIGE N,HSTTAB+<HTSIZE+NTSIZE>*2000
CAIL D,HSTTAB+HTSIZE*2000
JRST [MOVEI A,[ASCIZ/Host or network space allocs too small./]
PUSHJ P,ASZOUT
.VALUE]
SYSCAL RFNAME,[MOVEI INCH ? MOVEM A ? MOVEM FFN1 ? MOVEM FFN2 ? MOVEM FDIR]
.LOSE %LSSYS
SYSCAL SSTATU,[REPEAT 5,[ MOVEM FMCH ? ] MOVEM FMCH]
.LOSE %LSSYS
.CLOSE INCH,
RET
HSTTAB=600000
];IFN ITSSW
IFN T20SW,[
RHOSTF: SETZM HSTTAB ;init host table
MOVE A,[HSTTAB,,HSTTAB+1]
BLT A,<HSTTAB+UPSIZE*2000>-1
MOVE A,[440700,,HSTTAB+2000*<HTSIZE+NTSIZE>];rest is ASCIZ strings
MOVEM A,TOKBP'
MOVSI A,(GJ%SHT\GJ%OLD)
HRROI B,[ASCIZ/HOSTS.TXT/]
GTJFN
.VALUE
HRRZM A,INPJFN
MOVE B,[<70000,,0>\OF%RD]
OPENF
.VALUE
MOVEI D,HSTTAB ;Store indirect through D
MOVEI N,HSTTAB+HTSIZE*2000
CALL GHOST
MOVEM D,HSTTBE'
MOVEM N,NWKTBE'
CAIGE N,HSTTAB+<HTSIZE+NTSIZE>*2000
CAIL D,HSTTAB+HTSIZE*2000
JRST [MOVEI A,[ASCIZ/Host or network space allocs too small./]
PUSHJ P,ASZOUT
.VALUE]
SETO A,
CLOSF
.VALUE
RET
HSTTAB=400000 ;This must *NOT* change
];IFN T20SW
IFN SAILSW,[
RHOSTF: MOVEI A,<HSTTAB+UPSIZE*2000>-1 ;Moon sez: 6K should be enough core
CORE2 A, ;Make us an upper (NOTE: If this program is
.VALUE ;brought up on a Tops-10 this will have to change)
SETZM HSTTAB ;And at SAIL you ain't got no choice!
MOVE A,[HSTTAB,,HSTTAB+1]
BLT A,<HSTTAB+UPSIZE*2000>-1
MOVE A,[440700,,HSTTAB+2000*<HTSIZE+NTSIZE>];rest is ASCIZ strings
MOVEM A,TOKBP'
OPEN [0 ? 'DSK,, ? IBUFH]
.VALUE
DMOVE A,[SIXBIT/HOSTS/ ? 'TXT,,]
MOVE D,['NETMRC]
LOOKUP A
.VALUE
MOVEI D,HSTTAB ;Store indirect through D
MOVEI N,HSTTAB+HTSIZE*2000
CALL GHOST
MOVEM D,HSTTBE'
MOVEM N,NWKTBE'
CAIGE N,HSTTAB+<HTSIZE+NTSIZE>*2000
CAIL D,HSTTAB+HTSIZE*2000
JRST [MOVEI A,[ASCIZ/Host or network space allocs too small./]
PUSHJ P,ASZOUT
.VALUE]
CLOSE
RELEASE
RET
HSTTAB=400000 ;This must *NOT* change
];IFN SAILSW
NWKTAB=HSTTAB+2000*HTSIZE
OUTPT: OUTEND ;Pointer to where to put next word we add.
NAMP: 0 ;Addr of place to put NAME table
;(in our address space).
NAMEP: 0 ;Ptr for storing into NUMBERS table.
SITP: 0 ;Addr of place to put SITES table.
NETP: 0 ;Ptr for storing into NETWORK table.
NHOSTS: 0 ;Number of sites
NNETS: 0 ;Number of networks
NARPA: 0 ;Number of Arpanet addresses
NCHAOS: 0 ;Number of Chaos net addresses
NDIAL: 0 ;Number of Dialnet addresses
NWARPA: ASCIZ/ARPA/ ;Supported network names. All nets that we
NWCHAOS:ASCIZ/CHAOS/ ;know about must be here. THESE BETTER BE THE
NWDIAL: ASCIZ/DIAL/ ;SAME NAMES THAT ARE IN THE HOST TABLE!!!
NTARPA: 0 ;Pointers to NTRTAB entries for these nets
NTCHAOS:0
NTDIAL: 0
ADARPA: 0 ;Pointers to ADDRESS tables for these nets
ADCHAOS:0
ADDIAL: 0
IFN SAILSW,[
IBUFH: BLOCK 3 ;Input buffer header
];IFN SAILSW
IFN T20SW,[
INPJFN: BLOCK 1
];IFN T20SW
CONSTANTS
VARIABLES
;The data actually written into the file starts here.
OUT: SIXBIT /HOSTS2/ ;HSTSID
FFN1: ;HSTFN1 Include filenames of HOSTS file.
IFN ITSSW,0
.ELSE SIXBIT/HOSTS/
FFN2: ;HSTVRS
IFN ITSSW,0
IFN SAILSW,SIXBIT/SAIL/
IFN T20SW,SIXBIT/TOPS20/
FDIR: ;HSTDIR
IFN ITSSW,0
IFN SAILSW,SIXBIT/NETMRC/
IFN T20SW,SIXBIT/TOPS20/
FMCH: ;HSTMCH
IFN ITSSW,0
IFN SAILSW,SIXBIT/SAIL/
IFN T20SW,SIXBIT/TOPS20/
UNAME: 0 ;HSTWHO UNAME of person who compiles the file.
$DATE: 0 ;HSTDAT Date and time of compilation.
$TIME: 0 ;HSTTIM
NAMPR: 0 ;NAMPTR Pointer to NAME table, rel to OUT.
SITPR: 0 ;SITPTR Pointer to SITE table, rel to OUT.
NETPR: 0 ;NETPTR Pointer to NETWORK table, rel to OUT.
SYSNMS: ;The table of interned system and machine
;names starts here.
TIP: ASCIZ /TIP/ ;These are pre-interned so they go in known
PDP10: ASCIZ /PDP10/ ;places and are easy to test for in MACH.
ITS: ASCIZ /ITS/ ;Note: PDP10, not PDP-10, so fits in 1 word.
TENEX: ASCIZ /TENEX/
TOPS10: ASCIZ /TOPS-10/
TOPS20: ASCIZ /TOPS-20/
TEN50: ASCIZ /10-50/
TWENEX: ASCIZ /TWENEX/
BOTS10: ASCIZ /BOTTOMS-10/
SAIL: ASCIZ /WAITS/
PDP11: ASCIZ /PDP11/
ELF: ASCIZ /ELF/
UNIX: ASCIZ /UNIX/
RSX11: ASCIZ /RSX-11/
HYDRA: ASCIZ /HYDRA/
MULTIC: ASCIZ /MULTICS/
OUTEND=.
CORTOP=OUTEND+20*2000
FOO==.
CONSTANTS
VARIABLES
IFN .-FOO,Constants or variables in skeleton output file
END DUMP